home *** CD-ROM | disk | FTP | other *** search
- name msxtip
- ; File MSXTIP.ASM
- ; Last modification: 20 April 1986
-
- revlvl equ 6 ; Rev level 6, 13 April 1986
- ;;;REVLVL EQU 5 ;Revision level 6-25-85
-
- ;==============================================================================
- ;
- ; MSXTIPRO.ASM This file contains system dependent routines for the
- ; TI-Professional computer running MS-DOS version 2.10. This
- ; version features interrupt driven I/O and H19/Tektronix 4010
- ; emulation. This version has been tested at 9600 baud with
- ; no loss of data.
- ;
- ; Credits: Dan Smith Computing Center (303) 273-3396
- ; Colorado School of Mines
- ; Golden, Colorado 80241
- ; Joe Smith (now at TYMSHARE, 39100 Liberty St, Fremont CA 94538)
- ;
- ;==============================================================================
- ; Add global entry point vtstat for use by Status in mssset.
- ; Clear terminal emulation flag, flags.vtflg, in procedure lclini.
- ; Add register save/restore in procedure getbaud.
- ; Bump rev level to 6. Joe R. Doupnik 12 March 1986
- ; Add global procedures ihosts and ihostr to handle host initialization
- ; when packets are to be sent or received by us,resp. 24 March 1986
- ; Add global procedure dtrlow (without worker serhng) to force DTR & RTS low
- ; in support of Kermit command Hangup. Says Not Yet Implemented. [jrd]
- ; Add global procedure Dumpscr, called by Ter in file msster, to dump screen
- ; to a file. Just does a beep for now. 13 April 1986 [jrd]
- ; In proc Outchr add override of xon from chkxon sending routine.
- ; This makes a hand typed Xoff supress the xon flow control character sent
- ; automatically as the receiver buffer empties. 20 April 1986 [jrd]
-
- include mssdef.h
-
- public xofsnt, machnam, setktab, setkhlp, count
-
- public serini, serrst, clrbuf, outchr, coms, vts, vtstat, dodel
- public ctlu, cmblnk, locate, lclini, prtchr, dobaud, clearl
- public dodisk, getbaud, beep, puthlp, poscur, putmod, clrmod
- public sendbr, showkey
- public ihosts, ihostr, dtrlow, dumpscr ; [jrd]
-
- ;=========================================================================
- ; Data Segment variables for Ti-Pro
- ;
- ; external variables used:
- ; drives - # of disk drives on system
- ; flags - global flags as per flginfo structure defined in pcdefs
- ; portval - pointer to current portinfo structure (currently either port1
- ; or port2)
- ; port1, port2 - portinfo structures for the corresponding ports
- ;
- ; global variables defined in this module:
- ; xofsnt, xofrcv - tell whether we saw or sent an xoff.
- ;=========================================================================
-
- datas segment public 'datas'
-
- extrn drives:byte,flags:byte, dmpname:byte ; [jrd]
- extrn portval:word,port1:byte,port2:byte,port3:byte,port4:byte
-
- false equ 0
- true equ 1
- mntrgh equ bufsiz*3/4 ;High trigger point for XOFF
-
- machnam db 'TI-PRO (Revision ',REVLVL+'0',')$'
- badbd db cr,lf,'Unimplemented baud rate$'
- hngmsg db cr,lf,' The phone should have hungup.',cr,lf,'$' ; [jrd]
- hnghlp db cr,lf,' The modem control lines DTR and RTS for the current'
- db ' port are forced low (off)'
- db cr,lf,' to hangup the phone. Normally, Kermit leaves them'
- db ' high (on) when it exits.'
- db cr,lf,'$' ; [jrd]
- rdbuf db 80 dup (?) ; temp buf [jrd]
- noimp db cr,lf,'?Not implemented.$' ; [jrd]
- shkmsg db 'Not implemented.'
- shklen equ $-shkmsg
- setktab db 0 ;Must be defined. Used in Set Key command
- setkhlp db 0 ;Must be defined. Used in Set Key ?
- crlf db cr,lf,'$'
- delstr db bs,bs,' ',bs,'$';Delete string.
- clrlin db cr ;Must be at clreol-1
- clreol db esc,'[K$' ;Clear line.
- homeras db esc,'[H',esc,'[J$' ;Home and erase
- savint dw 0,0 ;Place to save interrupt vector
- invvid db esc,'[0;7m$' ;Inverse video
- norvid db esc,'[0;1m$' ;Normal video (WHITE=BOLD, as opposed to GREEN)
- xofsnt db 0 ;Say if we sent an XOFF.
- xofrcv db 0 ;Say if we received an XOFF.
- portin db 0 ;Non-zero if port is initialized
-
- source db bufsiz dup(?) ;Circular buffer for data from port
- savedi dw 0 ;Input pointer for circular buffer
- savesi dw 0 ;Output pointer for circular buffer
- count dw 0 ;Number of characters in buffer
-
- porttab db 04h ;4 entries
- db 01h,'1$'
- dw 01h
- db 01h,'2$'
- dw 02h ;*** NOTE: This is 2, not 0 ****
- db 01h,'3$'
- dw 03h
- db 01h,'4$'
- dw 04h
-
- ontab db 2 ;Number of entries
- db 03h,'OFF$'
- dw 0
- db 02h,'ON$'
- dw 1
-
- modem mdminfo <0e7h,0e6h,0e4h,0feh,001h,000h,40h*4> ;Init to Port 1 parms
-
- ; Data to init Serial Controller
- ; Channel A parameters
-
- parmta db 09h ;Select WR9
- db 0c0h ;Reset 8530
- db 0bh ;Select WR11
- db 50h ;No XTAL, RxC=BRG=TxC, TRxC pin is an input
- db 0eh ;Select WR14
- db 03h ;BRG source is PCLK pin, enable BRG
- db 0fh ;Select WR15
- db 0 ;Disable external status interrupts
- db 04h ;Select WR4
- db 44h ;x16 clock, 1 stop bit, no parity
- db 05h ;Select WR5
- db 11101010b ;Raise DTR+RTS, 8 bits, Tx enable
- db 03h ;Select WR3
- db 0c1h ;8 bits, enable receiver
- db 01h ;Select WR1
- db 10h ;Interrupt on all receive chars or spec. cond.
- db 9 ;Select WR9
- db 8 ;Master interrupt enable
- parmas equ $-parmta
-
- ; Channel B parameters
-
- parmtb db 0fh ;Select WR15
- db 00h ;Disable external status interrupts
- db 01h ;Select WR1
- db 00h ;Disable all other interrupts
- db 05h ;Select WR5
- db 02h ;Raise RTSB (RCNTL) for internal modem
- parmbs equ $-parmtb
-
- baudat label word ;Divisors for Z-8530 with 4.9152-MHz oscillator
- dw 0696h ; 0 45.5 baud
- dw 05FEh ; 1 50 baud
- dw 03FEh ; 2 75 baud
- dw 02B8h ; 3 110 baud (+0.03%)
- dw 0239h ; 4 134.5 baud (Selectric)
- dw 01FEh ; 5 150 baud
- dw 00FEh ; 6 300 baud
- dw 007Eh ; 7 600 baud
- dw 003Eh ; 8 1200 baud
- dw 0029h ; 9 1800 baud (-0.78%)
- dw 0024h ;10 2000 baud (+1.05%)
- dw 001Eh ;11 2400 baud
- dw 000Eh ;12 4800 baud
- dw 0006h ;13 9600 baud
- dw 0002h ;14 19.2 kbaud
- dw 0000h ;15 38.4 kbaud - not supported
- baudlen equ $-baudat ;Size of table in bytes
-
- datas ends
-
-
- ; Serial port routines -- Initialize
-
- code segment public 'code'
- assume cs:code,ds:datas
- extrn sleep:near ; [jrd]
- extrn comnd:near,dopar:near
-
- ;==============================================================================
- ; Initialization for using serial port. Returns normally.
- ; This is called for by SEND, RECEIVE, and CONNECT commands.
- ;==============================================================================
- db 'serini'
- serini proc near
- cmp portin,2 ;Is it initialized already?
- jz serinc ;Yes, skip all this
- cli ;Disable interrupts
- cld ;Do increments in string operations
- push es ;Set interrupt vector
- xor ax,ax
- mov es,ax ;Point to vector segment
- push bx ; save reg. [jrd]
- mov bx,modem.mdintv ;Get vector address for this com port
- mov ax,es:[bx]
- mov savint,ax ;Save old vector offset
- mov ax,offset serint
- mov es:[bx],ax ;Replace with my offset
- mov ax,es:[bx+2]
- mov savint+2,ax ;Save old vector segment
- mov es:[bx+2],cs ;Replace with my segment
- pop bx ; [jrd]
- pop es
- call clrbuf ;Clear 8530 and memory buffers
-
- mov si,offset parmta ;Addr of port A parameter table
- cmp portin,1 ;1 means reset but dont hang up modem
- jnz sini10
- add si,2 ;Skip over hardware reset to avoid
- ;hanging up TI internal modems
- sini10: mov dx,modem.mdstat ;Port A command/status addr
- in al,dx ;Make sure it's pointing to WR0
- mov cx,parmas ;Table size
- serina: lodsb ;Get a byte
- out dx,al ;Send it to 8530
- loop serina ;Do all of port A
-
- mov si,offset parmtb ;Addr of port-B parameter table
- mov dx,modem.mdcom ;Port B command/status addr
- in al,dx ;Make sure it's pointing to WR0
- mov cx,parmbs
- serinb: lodsb ;Get a byte
- out dx,al ;Send it to 8530
- loop serinb
-
- in al,19h ;Set up 8259a interrupt controller
- and al,modem.mden ;Enable IR0, IR1, IR2, or IR4
- out 19h,al
-
- sti ;Allow interrupts
- serinc: mov portin,2 ;Flag that port is set up
- ret
- serini endp
-
- ;==============================================================================
- ; Serial port interrupt handler. This routine gets all serial port interrupts
- ; and stores any data in a circular buffer.
- ;==============================================================================
- db 'serint'
- serint proc near
- sti ;Enable interrupts
- push ax ;Save registers used
- push bx
- push dx
- push di
- push ds
- push es
- cld ;Auto increment
- mov ax,seg datas
- mov ds,ax ;Set segment registers
- mov es,ax
- mov dx,modem.mdstat ;Get status register
- in al,dx ;Read RR0 contents
- and al,1 ;See if any characters in receive FIFO
- jz sint50 ;Jump if not
- mov dx,modem.mddat ;Point to data register
- in al,dx ;Get received character
- mov bx,portval ;Point to port data structure
- cmp [bx].parflg,parnon ;Is parity off?
- jz sint5 ;Jump if it is
- and al,7fh ;Strip off parity
- sint5: or al,al ;Throw away nulls
- jz sint50
- cmp [bx].floflg,0 ;Doing flow control?
- je sint20 ;No
- mov dx,[bx].flowc ;Flow control char, dh=XON, dl=XOFF
- cmp al,dl ;Is it an XOFF?
- jne sint10 ;No, go on
- mov xofrcv,1 ;Set flag
- jmp short sint50
- sint10: cmp al,dh ;Did we get an XON?
- jne sint20 ;No, go on
- mov xofrcv,0 ;Clear XOFF flag
- jmp short sint50
- sint20: mov di,savedi ;Point to buffer location
- stosb ;Store new char in circular buffer
- cmp di,offset source+bufsiz ;Is buffer pointer at end?
- jb sint30 ;No, carry on
- mov di,offset source ;Wrap buffer pointer to start of buffer
- sint30: inc count ;Increment number of chars in buffer
- cmp [bx].floflg,0 ;Doing flow control?
- je sint40 ;No, just leave
- cmp xofsnt,1 ;Have we sent an XOFF already?
- je sint40 ;Yes, don't send another
- cmp count,mntrgh ;Past the high trigger point?
- jbe sint40 ;No, the buffer still has room
- mov ah,dl ;Get the XOFF character
- call outchr ;Send it
- nop ;Waste 3 bytes for skip returns
- nop ; and ignore failures
- nop
- mov xofsnt,1 ;Remember we sent it
- sint40: mov savedi,di ;Update buffer pointer
- sint50: cli
- mov al,20h ;Get end of interrupt code
- out 18h,al ;Send End-of-Interrupt to 8259
- pop es ;Restore registers
- pop ds
- pop di
- pop dx
- pop bx
- pop ax
- iret
- serint endp
-
- ;==============================================================================
- ; Reset the serial port. This is the opposite of SERINI. Calling
- ; this twice without intervening calls to SERINI should be harmless.
- ; Returns normally.
- ;==============================================================================
- serrst proc near
- mov portin,1 ;1 means reset all but don't hangup
- cli ; internal modem
- mov dx,modem.mdstat ;Point to channel A WR0
- mov al,9
- out dx,al ;Register 9 write
- xor al,al
- nop
- out dx,al ;disable 8530 interrupts
- in al,19h ;Disable 8259a IR line
- or al,modem.mddis
- out 19h,al
- push es ;Reset interrupt vector
- push bx ; save reg. [jrd]
- xor bx,bx
- mov es,bx
- mov bx,modem.mdintv ;Get vector address
- mov ax,savint
- mov es:[bx],ax ;Restore saved vector
- mov ax,savint+2
- mov es:[bx+2],ax
- pop bx ; [jrd]
- pop es
- sti
- ret ;All done.
- serrst endp
-
- ;==============================================================================
- ; Clear the input buffer. This throws away all the characters in the
- ; serial interrupt buffer. This is particularly important when
- ; talking to servers, since NAKs can accumulate in the buffer.
- ;==============================================================================
- clrbuf proc near
- push ax ; save regs. [jrd]
- push cx
- push dx
- mov ax,offset source
- mov savedi,ax ;Place to put next character received
- mov savesi,ax ;Place to get next character from
- mov cx,8
- mov dx,modem.mddat ;Address channel-A data register
- clrbf1: in al,dx ;Clear out anything in the receive FIFO
- loop clrbf1
- mov count,cx ;Set count to zero
- pop dx
- pop cx
- pop ax
- ret
- clrbuf endp
-
- ;==============================================================================
- ; Put the char in AH to the serial port. This assumes the
- ; port has been initialized. Should honor xon/xoff. Skip returns on
- ; success, returns normally if the character cannot be written.
- ;==============================================================================
- db 'outchr'
- outchr proc near
- push bx
- push cx
- push dx
- mov bx,portval
- cmp [bx].floflg,0 ;Are we doing flow control.
- je outch2 ;No, just continue.
- xor cx,cx ;clear counter
- cmp ah,byte ptr [bp].flowc ; sending xoff? [jrd]
- jne outch1 ; ne = no
- mov xofsnt,false ; supress xon from chkxon buffer routine
- outch1: cmp xofrcv,1 ;Are we being held?
- jne outch2 ;No - it's OK to go on.
- loop outch1 ;held, try for a while
- mov xofrcv,0 ;timed out, force it off and fall thru.
- outch2: mov al,ah ;Parity routine works on AL.
- call dopar ;Set parity appropriately.
-
- mov ah,al ;Preserve character for a bit
- xor cx,cx ;Set loop counter to max
- mov dx,modem.mdstat ;Port 1 channel A command/status address
- outch3: in al,dx ;Get RR0 contents
- and al,04h ;Transmit buffer empty?
- jnz outch4 ;Yes, output char
- loop outch3 ;No, try again
- jmp outch5 ;Loop counter expired, give up
- outch4: mov dx,modem.mddat ;Get port 1 channel A data address
- mov al,ah ;Get the character
- out dx,al ;Send it
- pop dx
- pop cx
- pop bx
- jmp rskp ;Skip return for OK
-
- outch5: pop dx
- pop cx
- pop bx
- ret ;Non-skip return due to timeout
- outchr endp
-
- ;==============================================================================
- ; Set the current port. Called from SET PORT command
- ;==============================================================================
- coms proc near
- mov dx,offset porttab ;Point to list of port number keywords
- mov bx,0 ;No help
- mov ah,cmkey ;Parse a keyword
- call comnd
- jmp r ;Return for errors
- push bx ;Save port number
- mov ah,cmcfm
- call comnd ;Get a confirm.
- jmp comx ;Didn't get a confirm. error
- nop ;Need 3 bytes in here
- call serrst ;Reset previous serial port
- pop bx ;Restore desired comm port
- mov flags.comflg,bl ;Set the comm port flag.
-
- cmp flags.comflg,1 ;Port 1?
- jne coms2 ;No, try another
- mov portval,offset port1
- mov modem.mddat,0e7h ;Data reg
- mov modem.mdstat,0e6h ;Channel A command/status
- mov modem.mdcom,0e4h ;Channel B command/status
- mov modem.mddis,01h ;Mask to disable IR0
- mov modem.mden,0feh ;Mask to enable IR0
- mov modem.mdintv,40h*4 ;Vector for IR0
- call serini
- ret
-
- coms2: cmp flags.comflg,2 ;Port 2?
- jne coms3 ;No, try another
- mov portval,offset port2
- mov modem.mddat,0efh ;Data reg
- mov modem.mdstat,0eeh ;Channel A command/status
- mov modem.mdcom,0ech ;Channel B command/status
- mov modem.mddis,02h ;Mask to disable IR1
- mov modem.mden,0fdh ;Mask to enable IR1
- mov modem.mdintv,41h*4 ;Vector for IR1
- call serini
- ret
-
- coms3: cmp flags.comflg,3 ;Port 3?
- jne coms4 ;No, try another
- mov portval,offset port3
- mov modem.mddat,0f7h ;Data reg
- mov modem.mdstat,0f6h ;Channel A command/status
- mov modem.mdcom,0f4h ;Channel B command/status
- mov modem.mddis,04h ;Mask to disable IR2
- mov modem.mden,0fbh ;Mask to enable IR2
- mov modem.mdintv,42h*4 ;Vector for IR2
- call serini
- ret
-
- coms4: mov portval,offset port4
- mov modem.mddat,0ffh ;Data reg
- mov modem.mdstat,0feh ;Channel A command/status
- mov modem.mdcom,0fch ;Channel B command/status
- mov modem.mddis,10h ;Mask to disable IR4
- mov modem.mden,0efh ;Mask to enable IR4
- mov modem.mdintv,44h*4 ;Vector for IR4
- call serini
- ret
-
- comx: pop bx
- ret
- coms endp
-
- ;==============================================================================
- ; Set heath emulation on/off. Called from SET TERMINAL-EMULATION command
- ;==============================================================================
- vts proc near
- mov dx,offset ontab ;Table containing OFF ON keywords
- mov bx,0 ;No help
- mov ah,cmkey ;Means parse a keyword
- call comnd ;Parse for ON or OFF
- jmp r ;Jump for errors
- push bx ;Save returned code for ON or OFF
- mov ah,cmcfm ;Means parse a confirm
- call comnd ;Wait for confirm
- jmp short vt0 ;Jump for error
- nop ;Needs 3 bytes here
- pop bx ;Restore return status
- mov flags.vtflg,bl ;Set H19 on/off global variable
- ret
- vt0: pop bx
- ret
- vts endp
-
- VTSTAT PROC NEAR ; For Status display [jrd]
- ret ; no emulator status to display
- VTSTAT ENDP
-
- ; Save the screen to a buffer and then append buffer to a disk file. [jrd]
- ; Default filename is Kermit.scn; actual file can be a device too. Filename
- ; is determined by mssset and is passed as pointer dmpname.
-
- DUMPSCR PROC NEAR ; Dumps screen contents to a file. Just Beeps here
- call beep ; [jrd]
- ret
- DUMPSCR ENDP
-
-
- ;==============================================================================
- ; Delete a character from the terminal. This works by printing
- ; backspaces and spaces. Returns normally.
- ;==============================================================================
- dodel proc near
- mov ah,9
- mov dx,offset delstr ;Backspace-space-backspace
- int 21h
- ret
- dodel endp
-
- ;==============================================================================
- ; Move the cursor to the left margin, then clear to end of line.
- ; Returns normally.
- ;==============================================================================
- ctlu proc near
- mov ah,9
- mov dx,offset clrlin ;Output CR, then clear to end of line
- int 21h
- ret
- ctlu endp
-
- ;==============================================================================
- ; This routine blanks the screen. Returns normally.
- ;==============================================================================
- cmblnk proc near
- mov ah,13h ;Function 13h of INT 49h clears the screen
- int 49h
- ret
- cmblnk endp
-
- ;==============================================================================
- ; Homes the cursor. Returns normally.
- ;==============================================================================
- locate proc near
- xor dx,dx ;Go to top left corner of screen.
- jmp poscur
- locate endp
-
- ;==============================================================================
- ; Local initialization
- ;==============================================================================
- lclini proc near
- mov flags.vtflg,0 ; no terminal emulation. [jrd]
- call beep1 ;In case BASIC left the speaker messed up
- ret
- lclini endp
-
- ;==============================================================================
- ; Port read character. Check the port status. If no data, skip
- ; return. Else, read in a char and return.
- ;==============================================================================
- db 'prtchr'
- prtchr proc near
- call chkxon ;See if we need to XON first
- cmp count,0 ;See if anything in buffer
- jnz pc10 ;Jump if something there
- jmp rskp ;Skip return since nothing there
- pc10: mov si,savesi ;Get buffer pointer
- lodsb ;Get char from buffer
- cmp si,offset source+bufsiz ;See if past end of buffer
- jb pc20 ;Jump if not
- mov si,offset source ;Wrap pointer to start of buffer
- pc20: dec count ;1 less char in buffer
- mov savesi,si ;Save buffer pointer
- mov dx,count ;Return remaining count in DX
- ret
- prtchr endp
-
- ;==============================================================================
- ; Local routine to see if we have to transmit an xon
- ;==============================================================================
- chkxon proc near
- push bx
- mov bx,portval
- cmp [bx].floflg,0 ;Doing flow control?
- je chkxo1 ;No, skip all this
- cmp xofsnt,0 ;Have we sent an xoff?
- je chkxo1 ;No, forget it
- cmp count,mntrgh ;Below trigger?
- jae chkxo1 ;No forget it
- mov ax,[bx].flowc ;AH gets xon
- call outchr ;Send XON character
- nop
- nop
- nop ;In case it skips
- mov xofsnt,0 ;Remember we've sent the XON.
- chkxo1: pop bx ;Restore register
- ret ;And return
- chkxon endp
-
- ; IHOSTS - Initialize the host by sending XON, or equivalent, and enter the
- ; cycle of clear input buffer, wait 1 second, test if buffer empty then exit
- ; else repeat cycle. Requires that the port be initialized before hand.
- ; Ihosts is used by the local send-file routine just after initializing
- ; the serial port.
- ; 22 March 1986 [jrd]
-
- IHOSTS PROC NEAR
- push ax ; save the registers
- push bx
- push cx
- push dx
- mov bx,portval ; port indicator
- mov ax,[bx].flowc ; put Go-ahead flow control char in ah
- call outchr ; send it (release Host's output queue)
- nop ; outchr can do skip return
- nop
- nop
- ihosts1:call clrbuf ; clear out interrupt buffer
- mov ax,1 ; sleep for 1 second
- call sleep ; procedure sleep is in msscom.asm
- call prtchr ; check for char at port
- jmp ihosts1 ; have a char in al, repeat wait/read cycle
- nop ; prtchr does skip return on empty buffer
- pop dx ; empty buffer. we are done here.
- pop cx
- pop bx
- pop ax
- ret
- IHOSTS ENDP
-
- ; IHOSTR - initialize the remote host for our reception of a file by
- ; sending the flow-on character (XON typically) to release any held
- ; data. Called by receive-file code just after initializing the serial
- ; port. 22 March 1986 [jrd]
- IHOSTR PROC NEAR
- push ax ; save regs
- push bx
- push cx
- mov bx,portval ; port indicator
- mov ax,[bx].flowc ; put Go-ahead flow control char in ah
- call outchr ; send it (release Host's output queue)
- nop ; outchr can do skip return
- nop
- nop
- pop cx
- pop bx
- pop ax
- ret
- IHOSTR ENDP
-
- DTRLOW PROC NEAR ; Global proc to Hangup the Phone by making
- ; DTR and RTS low.
- mov ah,cmtxt ; allow text to be able to display help
- mov bx,offset rdbuf ; dummy buffer
- mov dx,offset hnghlp ; help message
- call comnd ; get a confirm
- jmp r
- ; not yet imp. call serhng ; drop DTR and RTS
- mov ah,prstr ; give a nice message
- ; not yet imp. mov dx,offset hngmsg
- mov dx,offset noimp ; for now
- int dos
- jmp rskp
- DTRLOW ENDP
-
- ; Hang up the Phone. Similar to SERRST except it just forces DTR and RTS low
- ; to terminate the connection. 29 March 1986 [jrd]
- ; Calling this twice without intervening calls to serini should be harmless.
- ; Returns normally.
- ; SERHNG is Not Yet Implemented.
-
-
- ;==============================================================================
- ; Set the baud rate for the current port, based on the value
- ; in the portinfo structure. Returns normally.
- ; Called from SET BAUD command with new index in PORT.BAUD, previous in AX
- ;==============================================================================
- db 'dobaud'
- dobaud proc near
- push bx
- mov bx,portval ;Get pointer
- mov bx,[bx].baud ;Get new baud-rate index
- shl bx,1 ;Multiply by 2
- cmp baudat[bx],0 ;Test for zero
- jne dobod1 ;Nonzero is OK
- mov bx,portval ;Error, get back to data structure
- mov [bx].baud,ax ;Restore previous baud rate number
- mov ah,9
- mov dx,offset badbd ;Bad baud rate
- int 21h
- pop bx
- ret
-
- dobod1: mov ax,baudat[bx] ;Get BRG divisor
- call setbaud ;Send AX to baud-rate-divisor
- pop bx
- ret
- dobaud endp
-
- ;==============================================================================
- ; Local routine to send AX to the Baud Rate Generator. Preserves all regs
- ;==============================================================================
- setbaud proc near
- push dx
- push ax ;Save rate
- mov dx,modem.mdstat ;Address the channel-A command port
- mov al,13 ;Point to register 13
- out dx,al
- jmp short $+2 ;Slight delay to let hardware respond
- mov al,ah ;High-order part of divisor
- out dx,al
- jmp short $+2
- mov al,12 ;Point to register 12
- out dx,al
- jmp short $+2
- pop ax
- out dx,al ;Low-order part of divisor
- pop dx
- ret
- setbaud endp
-
- ;==============================================================================
- ; Clear to the end of the current line. Returns normally.
- ;==============================================================================
- clearl proc near
- mov ah,9
- mov dx,offset clreol ;Erase from cursor to end of line
- int 21h
- ret
- clearl endp
-
- ;==============================================================================
- ; this is called by Kermit initialization. It checks the
- ; number of disks on the system, sets the drives variable
- ; appropriately. Returns normally.
- ;==============================================================================
- dodisk proc near
- mov ah,gcurdsk ;Current disk value to AL.
- int 21h
- mov dl,al ;Put current disk in DL.
- mov ah,seldsk ;Select current disk.
- int 21h ;Returns number of drives in AL.
- mov drives,al ;Set global variable
- ret
- dodisk endp
-
- ;==============================================================================
- ; Get the current baud rate from the serial card and set it
- ; in the portinfo structure for the current port. Returns normally.
- ; This is used during initialization.
- ;==============================================================================
- getbaud proc near
- push ax ; save some regs. [jrd]
- push bx ; [jrd]
- push dx ; [jrd]
- mov dx,modem.mdstat ;Address channel-A command port
- mov al,13 ;Point to register 13
- out dx,al
- jmp short $+2 ;Small delay
- in al,dx ;Read RR13
- mov ah,al ;Save high-order part
- mov al,12 ;Point to register 12
- out dx,al
- jmp short $+2
- in al,dx ;Read RR12
- ;Baud rate = (300*256)/(AX+2)
- mov bx,0 ;Index value
- getbd1: cmp ax,baudat[bx] ;See if known value
- je getbd2 ;Found it
- add bx,2 ;Point to next word
- cmp bl,baudlen ;End of table?
- jl getbd1 ;No, keep looking
- mov bx,B1200*2 ;Yes, force it to 1200 baud
- mov ax,baudat[bx]
- call setbaud
-
- getbd2: mov ax,bx ;Get the byte index
- shr ax,1 ;Reduce to number from 0 to 15
- mov bx,portval ;Point to structure
- mov [bx].baud,ax ;Store where SHOW processor can see it
- pop dx ; restore regs. [jrd]
- pop bx ; [jrd]
- pop ax ; [jrd]
- ret
- getbaud endp
-
- ;==============================================================================
- ; Produce a short beep. The PC DOS bell is long enough to cause a loss
- ; of data at the port. Returns normally.
- ;==============================================================================
- beep1 proc near
- mov ah,2 ;Set speaker frequency
- mov cx,1000 ;Approx 1.5 kHz
- int 48h
- ret
- beep1 endp
-
- beep proc near
- call beep1 ;Set the frequency
- mov ah,0 ;Timed beep function
- mov al,5 ;5/40 = 1/8 second
- int 48h
- ret
- beep endp
-
- ;==============================================================================
- ; Put a help message on the screen.
- ; Pass the message in ax, terminated by a null. Returns normally.
- ;==============================================================================
- puthlp proc near
- push ax ;preserve this
- mov ah,9
- mov dx,offset crlf
- int 21h
- pop si ;point to string again
- puthl3: lodsb ;get a byte
- cmp al,0 ;end of string?
- je puthl4 ;yes, stop
- mov dl,al
- mov ah,6
- int 21h ;else write to screen
- jmp puthl3 ;and keep going
- puthl4: mov ah,9
- mov dx,offset crlf
- int 21h
- ret
- puthlp endp
-
- ;==============================================================================
- ; Write a line at the bottom of the screen...
- ; the line is passed in dx, terminated by a $. Returns normally.
- ;==============================================================================
- putmod proc near
- push dx ;preserve message
- mov dx,24*100h ;now address line 24
- call poscur
- mov dx,offset invvid
- mov ah,9
- int 21h ;Set inverse video
- pop dx ;get message back
- mov ah,9
- int 21h ;write it out
- mov dx,offset norvid
- mov ah,9
- int 21h ;Normal video
- ret ;and return
- putmod endp
-
- ;==============================================================================
- ; Clear the mode line written by PUTMOD. Returns normally.
- ;==============================================================================
- clrmod proc near
- mov dx,1800h
- call poscur ;Go to bottom row.
- call clearl ;Clear to end of line.
- ret
- clrmod endp
-
- ;==============================================================================
- ; Position the cursor according to contents of DX:
- ; DH contains row, DL contains column. Returns normally.
- ;==============================================================================
- poscur proc near
- xchg dh,dl ;BIOS wants row in DL, Col in DH
- mov ah,2 ;Locate cursor function
- int 49h
- ret
- poscur endp
-
- ;==============================================================================
- ; Send a break out the current serial port. Returns normally.
- ;==============================================================================
- sendbr proc near
- push cx
- push dx
- push ax
- xor cx,cx ;Clear loop counter.
- mov dx,modem.mdstat ;Address channel-A command port
- mov al,5 ;Point to register 5
- out dx,al
- jmp short $+2
- in al,dx ;Get current setting.
- mov ah,al ;Copy the bits
- mov al,5 ;Point back to register 5
- out dx,al
- mov al,ah ;Get old bits
- or al,10h ;Set send-break bit
- out dx,al ;Start the break
- pause: loop pause ;Wait a while.
- mov al,5 ;Point to register 5
- out dx,al
- jmp short $+2
- mov al,ah ;Clear send-break bit
- out dx,al ;Stop the break
- pop ax
- pop dx
- pop cx
- ret ;And return.
- ret
- sendbr endp
-
- ;==============================================================================
- ; Called by the SHOW KEY command
- ;==============================================================================
- showkey proc near
- mov ax,offset shkmsg
- mov cx,shklen
- ret
- showkey endp
-
- ;==============================================================================
- ; Jumping to this location is like retskp. It assumes the instruction
- ; after the call is a jmp addr.
- ;==============================================================================
- rskp proc near
- pop bp
- add bp,3
- push bp
- ret
- rskp endp
-
- ;==============================================================================
- ; Jumping here is the same as a ret. The jump to here uses up the 3 bytes
- ;==============================================================================
- r proc near
- ret
- r endp
-
- code ends
- end
-